home *** CD-ROM | disk | FTP | other *** search
/ Cream of the Crop 26 / Cream of the Crop 26.iso / os2 / octa209s.zip / octave-2.09 / libcruft / lapack / dorgtr.f < prev    next >
Text File  |  1997-06-25  |  5KB  |  164 lines

  1.       SUBROUTINE DORGTR( UPLO, N, A, LDA, TAU, WORK, LWORK, INFO )
  2. *
  3. *  -- LAPACK routine (version 2.0) --
  4. *     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
  5. *     Courant Institute, Argonne National Lab, and Rice University
  6. *     September 30, 1994
  7. *
  8. *     .. Scalar Arguments ..
  9.       CHARACTER          UPLO
  10.       INTEGER            INFO, LDA, LWORK, N
  11. *     ..
  12. *     .. Array Arguments ..
  13.       DOUBLE PRECISION   A( LDA, * ), TAU( * ), WORK( LWORK )
  14. *     ..
  15. *
  16. *  Purpose
  17. *  =======
  18. *
  19. *  DORGTR generates a real orthogonal matrix Q which is defined as the
  20. *  product of n-1 elementary reflectors of order N, as returned by
  21. *  DSYTRD:
  22. *
  23. *  if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
  24. *
  25. *  if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
  26. *
  27. *  Arguments
  28. *  =========
  29. *
  30. *  UPLO    (input) CHARACTER*1
  31. *          = 'U': Upper triangle of A contains elementary reflectors
  32. *                 from DSYTRD;
  33. *          = 'L': Lower triangle of A contains elementary reflectors
  34. *                 from DSYTRD.
  35. *
  36. *  N       (input) INTEGER
  37. *          The order of the matrix Q. N >= 0.
  38. *
  39. *  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
  40. *          On entry, the vectors which define the elementary reflectors,
  41. *          as returned by DSYTRD.
  42. *          On exit, the N-by-N orthogonal matrix Q.
  43. *
  44. *  LDA     (input) INTEGER
  45. *          The leading dimension of the array A. LDA >= max(1,N).
  46. *
  47. *  TAU     (input) DOUBLE PRECISION array, dimension (N-1)
  48. *          TAU(i) must contain the scalar factor of the elementary
  49. *          reflector H(i), as returned by DSYTRD.
  50. *
  51. *  WORK    (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
  52. *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  53. *
  54. *  LWORK   (input) INTEGER
  55. *          The dimension of the array WORK. LWORK >= max(1,N-1).
  56. *          For optimum performance LWORK >= (N-1)*NB, where NB is
  57. *          the optimal blocksize.
  58. *
  59. *  INFO    (output) INTEGER
  60. *          = 0:  successful exit
  61. *          < 0:  if INFO = -i, the i-th argument had an illegal value
  62. *
  63. *  =====================================================================
  64. *
  65. *     .. Parameters ..
  66.       DOUBLE PRECISION   ZERO, ONE
  67.       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
  68. *     ..
  69. *     .. Local Scalars ..
  70.       LOGICAL            UPPER
  71.       INTEGER            I, IINFO, J
  72. *     ..
  73. *     .. External Functions ..
  74.       LOGICAL            LSAME
  75.       EXTERNAL           LSAME
  76. *     ..
  77. *     .. External Subroutines ..
  78.       EXTERNAL           DORGQL, DORGQR, XERBLA
  79. *     ..
  80. *     .. Intrinsic Functions ..
  81.       INTRINSIC          MAX
  82. *     ..
  83. *     .. Executable Statements ..
  84. *
  85. *     Test the input arguments
  86. *
  87.       INFO = 0
  88.       UPPER = LSAME( UPLO, 'U' )
  89.       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  90.          INFO = -1
  91.       ELSE IF( N.LT.0 ) THEN
  92.          INFO = -2
  93.       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  94.          INFO = -4
  95.       ELSE IF( LWORK.LT.MAX( 1, N-1 ) ) THEN
  96.          INFO = -7
  97.       END IF
  98.       IF( INFO.NE.0 ) THEN
  99.          CALL XERBLA( 'DORGTR', -INFO )
  100.          RETURN
  101.       END IF
  102. *
  103. *     Quick return if possible
  104. *
  105.       IF( N.EQ.0 ) THEN
  106.          WORK( 1 ) = 1
  107.          RETURN
  108.       END IF
  109. *
  110.       IF( UPPER ) THEN
  111. *
  112. *        Q was determined by a call to DSYTRD with UPLO = 'U'
  113. *
  114. *        Shift the vectors which define the elementary reflectors one
  115. *        column to the left, and set the last row and column of Q to
  116. *        those of the unit matrix
  117. *
  118.          DO 20 J = 1, N - 1
  119.             DO 10 I = 1, J - 1
  120.                A( I, J ) = A( I, J+1 )
  121.    10       CONTINUE
  122.             A( N, J ) = ZERO
  123.    20    CONTINUE
  124.          DO 30 I = 1, N - 1
  125.             A( I, N ) = ZERO
  126.    30    CONTINUE
  127.          A( N, N ) = ONE
  128. *
  129. *        Generate Q(1:n-1,1:n-1)
  130. *
  131.          CALL DORGQL( N-1, N-1, N-1, A, LDA, TAU, WORK, LWORK, IINFO )
  132. *
  133.       ELSE
  134. *
  135. *        Q was determined by a call to DSYTRD with UPLO = 'L'.
  136. *
  137. *        Shift the vectors which define the elementary reflectors one
  138. *        column to the right, and set the first row and column of Q to
  139. *        those of the unit matrix
  140. *
  141.          DO 50 J = N, 2, -1
  142.             A( 1, J ) = ZERO
  143.             DO 40 I = J + 1, N
  144.                A( I, J ) = A( I, J-1 )
  145.    40       CONTINUE
  146.    50    CONTINUE
  147.          A( 1, 1 ) = ONE
  148.          DO 60 I = 2, N
  149.             A( I, 1 ) = ZERO
  150.    60    CONTINUE
  151.          IF( N.GT.1 ) THEN
  152. *
  153. *           Generate Q(2:n,2:n)
  154. *
  155.             CALL DORGQR( N-1, N-1, N-1, A( 2, 2 ), LDA, TAU, WORK,
  156.      $                   LWORK, IINFO )
  157.          END IF
  158.       END IF
  159.       RETURN
  160. *
  161. *     End of DORGTR
  162. *
  163.       END
  164.